GrowLeaf Subroutine

private subroutine GrowLeaf(npp, af, Ta, Tcold, swc, swp, sfc, tr, sla, mleaf, lai)

update leaf biomass and leaf area index

References:

Maneta, M. P., and N. L. Silverman, 2013: A spatially distributed model to simulate water, energy, and vegetation dynamics using information from regional climate models. Earth Interact., 17 doi:10.1175/2012EI000472.1.

Arora, V. K., and G. J. Boer, 2005: A parameterization of leaf phenology for the terrestrial ecosystem component of climate models. Global Change Biol., 11, 39–59.

Arguments

Type IntentOptional Attributes Name
real(kind=float), intent(in) :: npp

net primary production [t/ha]

real(kind=float), intent(in) :: af

allocation factor [0-1]

real(kind=float), intent(in) :: Ta

air temperature [°C]

real(kind=float), intent(in) :: Tcold

temperature threshold that accelerates leaf turnover (°C)

real(kind=float), intent(in) :: swc

soil water content [m3/m3]

real(kind=float), intent(in) :: swp

soil wilting point [m3/m3]

real(kind=float), intent(in) :: sfc

soil field capacity [m3/m3]

real(kind=float), intent(in) :: tr

leaf turnover rate [s-1]

real(kind=float), intent(in) :: sla

specific leaf area [m2/Kg]

real(kind=float), intent(inout) :: mleaf

mass of leaf [t/ha]

real(kind=float), intent(inout) :: lai

leaf area index [m2/m2]


Variables

Type Visibility Attributes Name Initial
real(kind=float), public :: actual_tr

actual leaf tirnover rate with temperature and soil water content stresses

real(kind=float), public :: deltaMleaf

leaf mass increment

real(kind=float), public :: swc_stress

soil water content stress that affects leaf increment [0-1]

real(kind=float), public :: temp_stress

temperature stress that affects leaf increment [0-1]


Source Code

SUBROUTINE  GrowLeaf &
!
(npp, af, Ta, Tcold, swc, swp, sfc, tr, sla, mleaf, lai) 

IMPLICIT NONE

!arguments with intent(in):
REAL (KIND = float), INTENT(IN) :: npp !!net primary production [t/ha]
REAL (KIND = float), INTENT(IN) :: af !!allocation factor [0-1]
REAL (KIND = float), INTENT(IN) :: Ta !! air temperature [°C]
REAL (KIND = float), INTENT(IN) :: Tcold !! temperature threshold that accelerates leaf turnover (°C)
REAL (KIND = float), INTENT(IN) :: swc !! soil water content [m3/m3]
REAL (KIND = float), INTENT(IN) :: swp !! soil wilting point [m3/m3]
REAL (KIND = float), INTENT(IN) :: sfc !! soil field capacity [m3/m3]
REAL (KIND = float), INTENT(IN) :: tr !! leaf turnover rate [s-1]
REAL (KIND = float), INTENT(IN) :: sla !! specific leaf area  [m2/Kg]

!arguments with intent(inout):
REAL (KIND = float), INTENT(INOUT) :: mleaf !!mass of leaf [t/ha]
REAL (KIND = float), INTENT(INOUT) :: lai !! leaf area index [m2/m2]

!local declarations:
REAL (KIND = float) :: deltaMleaf !! leaf mass increment
REAL (KIND = float) :: swc_stress !! soil water content stress that affects leaf increment [0-1]
REAL (KIND = float) :: temp_stress !! temperature stress that affects leaf increment [0-1]
REAL (KIND = float) :: actual_tr !! actual leaf tirnover rate with temperature and soil water content stresses

!------------------------------end of declarations----------------------------

!compute temperature stress
IF (Ta >= Tcold) THEN
    temp_stress = 1.
ELSE IF ((Tcold - 5.) < Ta < Tcold) THEN
    temp_stress = (Ta - Tcold - 5.) / 5.
ELSE IF (Ta <= (Tcold - 5.)) THEN
    temp_stress = 0.
END IF
!temp_stress = MAX (0., MIN (1., ((Ta - (Tcold - 5.) / 5. ) ) ))

!compute hydrologic stress
swc_stress = MAX (0., MIN (1., (swc - swp) / (sfc - swp) ) )  

!compute actual leaf turnover rate: base turnover + 0.001 hydrologic stress + temperature stress
actual_tr = tr * ( 1. + 0.001 * (1. - swc_stress)**3. + (1. - temp_stress)**3. )

!leaf mass increment
deltaMleaf = af * npp 

!update leaf biomass
mleaf = mleaf + deltaMleaf
             
!update leaf area index
lai = lai + (deltaMleaf * sla/ 10.) -  (actual_tr * dtPlants) *LAI !10 = conversion factor 1000 [kg/t] / 10000 [m2/hectare]

!check lower boundary
IF (mleaf < 0.) THEN
    mleaf = 0.
END IF

IF (lai < 0.) THEN
    lai = 0.
END IF

RETURN
END SUBROUTINE GrowLeaf